home *** CD-ROM | disk | FTP | other *** search
/ Language/OS - Multiplatform Resource Library / LANGUAGE OS.iso / smaltalk / st80_pr4.lha / st80_pre4 / Foible / foible / BinIO.st < prev    next >
Text File  |  1993-07-24  |  18KB  |  630 lines

  1. 'From Smalltalk-80, Version 2.3 of 13 June 1988 on 4 October 1989 at 3:01:23 pm'!
  2.  
  3.  
  4. !SmallInteger methodsFor: 'binary storage'!
  5.  
  6. hasSpecialBinaryRepresentation
  7.     ^true!
  8.  
  9. storeBinaryOn: stream manager: manager
  10.     "SmallIntegers are stored as their value with the 32nd bit set as a tag."
  11.  
  12.     stream
  13.         nextPut: (((self bitShift: -24) bitAnd: 16rFF) bitOr: 16r80);
  14.         nextPut: ((self bitShift: -16) bitAnd: 16rFF);
  15.         nextPut: ((self bitShift: -8) bitAnd: 16rFF);
  16.         nextPut: (self bitAnd: 16rFF)! !
  17.  
  18.  
  19. !String methodsFor: 'binary storage'!
  20.  
  21. storeBinaryDefinitionOn: stream manager: manager
  22.     manager putIdOf: self class on: stream.
  23.     stream nextNumber: 4 put: self basicSize.
  24.     stream nextPutAll: self asByteArray! !
  25.  
  26.  
  27. !Form methodsFor: 'binary storage'!
  28.  
  29. readBinaryContentsFrom: stream manager: manager
  30.     "read the trailing byte containing flags to define system dependent information about the form
  31.      and respond accordingly.  No flags are currently set."
  32.  
  33.     | flags |
  34.     super readBinaryContentsFrom: stream manager: manager.
  35.     flags _ stream next!
  36.  
  37. storeBinaryDefinitionOn: stream manager: manager
  38.     "append a byte containing flags to define system dependent information about the form.
  39.      Currently, no bits are set."
  40.  
  41.     super storeBinaryDefinitionOn: stream manager: manager.
  42.     stream nextPut: 0! !
  43.  
  44.  
  45. !Object methodsFor: 'testing'!
  46.  
  47. isClass
  48.     ^false!
  49.  
  50. isFileStream
  51.     ^false! !
  52.  
  53. !Object methodsFor: 'public binary storage'!
  54.  
  55. storeBinary
  56.     "Writes a description of the receiver into a file, in a way that allows
  57.      the object's structure to be reconstructed from the file's contents."
  58.  
  59.     | fileName |
  60.     fileName _ FileDirectory
  61.                     requestFileName: 'Store binary on which file name?'
  62.                     default: (self class name, '.', self asOop printString, '.stbin')
  63.                     version: #any
  64.                     ifFail: [^nil].
  65.     BinaryOutputManager store: self on: fileName!
  66.  
  67. storeBinaryOn: aStream
  68.     "Writes a description of the receiver onto aStream, in a way that allows
  69.      the object's structure to be reconstructed from the stream's contents"
  70.  
  71.     BinaryOutputManager store: self on: aStream! !
  72.  
  73. !Object methodsFor: 'binary storage'!
  74.  
  75. hasSpecialBinaryRepresentation
  76.     ^false!
  77.  
  78. readBinaryContentsFrom: stream manager: manager
  79.     | size i |
  80.     size _ self class instSize.
  81.     i _ 0.
  82.     [(i _ i + 1) <= size] whileTrue: [
  83.         self instVarAt: i put: manager nextObject].
  84.     size _ self basicSize.
  85.     i _ 0.
  86.     [(i _ i + 1) <= size] whileTrue: [
  87.         self basicAt: i put: manager nextObject]!
  88.  
  89. storeBinaryDefinitionOn: stream manager: manager
  90.  
  91.     | i basicSize instSize |
  92.     manager putIdOf: self class on: stream.
  93.     i _ 0.
  94.     self class isPointers
  95.         ifTrue: [
  96.             stream nextPut: (instSize _ self class instSize).
  97.             self class isVariable
  98.                 ifTrue: [stream nextNumber: 3 put: (basicSize _ self basicSize)]
  99.                 ifFalse: [basicSize _ 0].
  100.  
  101.             [(i _ i + 1) <= instSize] whileTrue: [
  102.                 manager putIdOf: (self instVarAt: i) on: stream].
  103.  
  104.             i _ 0.
  105.             [(i _ i + 1) <= basicSize] whileTrue: [
  106.                 manager putIdOf: (self basicAt: i) on: stream]]
  107.         ifFalse: [
  108.             stream nextNumber: 4 put: (basicSize _ self basicSize).
  109.             self class isBytes
  110.                 ifTrue: [
  111.                     [(i _ i + 1) <= basicSize] whileTrue: [
  112.                         stream nextPut: (self basicAt: i)]]
  113.                 ifFalse: [
  114.                     [(i _ i + 1) <= basicSize] whileTrue: [
  115.                         stream nextWordPut: (self basicAt: i)]]]!
  116.  
  117. storeBinaryOn: stream manager: manager
  118.     manager putIdOf: self on: stream! !
  119.  
  120.  
  121. !ExternalStream methodsFor: 'nonhomogeneous accessing'!
  122.  
  123. nextNumber: n 
  124.     "Answer the next n bytes as a positive Integer or LargePositiveInteger."
  125.  
  126.     | s i |
  127.     n <= 4 ifTrue: 
  128.         [s _ 0.
  129.         i _ 0.
  130.         [(i _ i + 1) <= n] whileTrue: [s _ ((s bitShift: 8) bitOr: self next)].
  131.         ^s].
  132.     s _ LargePositiveInteger new: n.
  133.     1 to: n do: [:j | s at: n + 1 - j put: self next].
  134.     "reverse order of significance"
  135.     ^s truncated!
  136.  
  137. nextNumber: n put: v 
  138.     "Append to the receiver the argument, v, which is a positive SmallInteger or
  139.     a LargePositiveInteger, as the next n bytes.  Possibly pad with leading zeros."
  140.  
  141.     | vlen i |
  142.     n < (vlen _ v digitLength) ifTrue: [self error: 'number too big'].
  143.  
  144.     "pad with leading zeros"
  145.     i _ n.
  146.     [i > vlen] whileTrue: [self nextPut: 0. i _ i - 1].
  147.     i = 1 ifTrue: [^self nextPut: v].
  148.     [i > 0] whileTrue: [self nextPut: (v digitAt: i). i _ i - 1]! !
  149.  
  150.  
  151. !SmallInteger class methodsFor: 'binary storage'!
  152.  
  153. binaryDefinitionFrom: stream manager: manager
  154.     | value |
  155.     (value _ (stream next bitAnd: 16r7F)) > 16r3F
  156.         ifTrue: [value _ value - 16r80].
  157.     value _ (value bitShift: 8) bitOr: stream next.
  158.     value _ (value bitShift: 8) bitOr: stream next.
  159.     value _ (value bitShift: 8) bitOr: stream next.
  160.     ^value! !
  161.  
  162.  
  163. !TextStyle class methodsFor: 'binary storage'!
  164.  
  165. addGlobalsTo: globalDictionary manager: manager
  166.     TextStyles do: [:style|
  167.         style fontArray do: [:font|
  168.             globalDictionary at: font put: self]]!
  169.  
  170. storeBinaryDefinitionOf: anObject on: stream manager: manager
  171.     | style string |
  172.     anObject class == StrikeFont ifTrue: [
  173.         TextStyles associationsDo: [:assoc|
  174.             style _ assoc value.
  175.             1 to: style fontArray size do: [:i|
  176.                 (style fontAt: i) == anObject ifTrue: [
  177.                     string _ '(TextStyle styleNamed: ', assoc key storeString, ') fontAt: ', i printString.
  178.                     stream nextNumber: 2 put: string size.
  179.                     string do: [:char| stream nextPut: char asciiValue].
  180.                     ^self]]]].
  181.     ^super storeBinaryDefinitionOf: anObject on: stream manager: manager! !
  182.  
  183. IdentityDictionary variableSubclass: #BinaryIOManager
  184.     instanceVariableNames: ''
  185.     classVariableNames: 'ClassType FalseType GlobalType IdType NilType ObjectType TrueType TypeTable '
  186.     poolDictionaries: ''
  187.     category: 'System-Support'!
  188. BinaryIOManager comment:
  189. 'I am a shared superclass for the binary IO classes BinaryInputManager & BinaryOutputManager.
  190. I define some class variables that define the types of descriptions in binary files, see BinaryIOManager class>>initialize'!
  191.  
  192.  
  193. !BinaryIOManager methodsFor: 'accessing'!
  194.  
  195. codeForFalse
  196.     ^FalseType!
  197.  
  198. codeForNil
  199.     ^NilType!
  200.  
  201. codeForTrue
  202.     ^TrueType! !
  203.  
  204. !BinaryIOManager methodsFor: 'adding'!
  205.  
  206. grow
  207.     "Must copy instance variables when growing"
  208.     | instVars |
  209.     instVars _ (self class superclass instSize + 1 to: self class instSize) collect: [:i|
  210.                     Association key: i value: (self instVarAt: i)].
  211.     super grow.
  212.     instVars do: [:assoc| self instVarAt: (assoc key) put: assoc value]! !
  213.  
  214. !BinaryIOManager methodsFor: 'private'!
  215.  
  216. rehash
  217.     "Must copy instance variables when rehashing"
  218.     | instVars |
  219.     instVars _ (self class superclass instSize + 1 to: self class instSize) collect: [:i|
  220.                     Association key: i value: (self instVarAt: i)].
  221.     super rehash.
  222.     instVars do: [:assoc| self instVarAt: (assoc key) put: assoc value]! !
  223. "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
  224.  
  225. BinaryIOManager class
  226.     instanceVariableNames: ''!
  227.  
  228.  
  229. !BinaryIOManager class methodsFor: 'class initialization'!
  230.  
  231. initialize
  232.     "Initialize the types & type table for binary i/o"
  233.  
  234.     TypeTable _ #(    getObjectId
  235.                         getNil
  236.                         getTrue
  237.                         getFalse
  238.                         getObjectDefinition
  239.                         getClassDefinition
  240.                         getGlobalDefinition ).
  241.     IdType _ 1.
  242.     NilType _ 2.
  243.     TrueType _ 3.
  244.     FalseType _ 4.
  245.     ObjectType _ 5.
  246.     ClassType _ 6.
  247.     GlobalType  _ 7
  248.  
  249.     "BinaryIOManager initialize"! !
  250.  
  251. BinaryIOManager initialize!
  252.  
  253.  
  254. BinaryIOManager variableSubclass: #BinaryOutputManager
  255.     instanceVariableNames: 'lastIndex globals '
  256.     classVariableNames: ''
  257.     poolDictionaries: ''
  258.     category: 'System-Support'!
  259. BinaryOutputManager comment:
  260. 'Binary storage consists of a sequence of Object IDs
  261.  
  262. Object IDs are identified by 4 byte words.
  263. First byte defines type:
  264.  
  265. byte between: 128 and: 255
  266.         small integer in 31 bits
  267.  
  268. byte = 0        object id in next 3 bytes
  269. byte = 1        nil
  270. byte = 2        true
  271. byte = 3        false
  272. byte = 4        object id in next 3 bytes; object definition follows
  273. byte = 5        class id in next 3 bytes; class definition follows
  274. byte = 6        global id in next 3 bytes; global definition follows
  275.  
  276. Object Definitions are
  277.     class id
  278.     followed by
  279.         non-indexable
  280.             inst size in next byte
  281.             ''inst size'' ids follow
  282.         indexable
  283.             inst size in next byte
  284.             variable size in next 3 bytes
  285.             ''inst size'' ids follow
  286.             ''variable size'' elements follow
  287.  
  288.     see implementors of storeBinaryDefinitionOn:manager: & readBinaryContentsFrom:manager:
  289.  
  290. Class Definitions are
  291.         format in next 2 bytes
  292.         name length in next 2 bytes
  293.         name length bytes of name
  294.  
  295. Global Definitions are
  296.     expression length in next two bytes
  297.     ''expression'' characters follow
  298.  
  299.  
  300. The objects stored as global definitions are collected during BinaryOutputManager>>initialize using the addGlobalsTo:manager: message.  It is possible (hopefully easily) to customize this to add your own globals to the set.'!
  301.  
  302.  
  303. !BinaryOutputManager methodsFor: 'initialize-release'!
  304.  
  305. initialize
  306.     "Initialize my self for subsequent binary output of some object."
  307.     lastIndex _ 0.
  308.     globals _ IdentityDictionary new: 2048.
  309.  
  310.     "Get the system (Smalltalk) to register all objects it considers 'global'
  311.      to the globals table.  Such objects will not be stored; instead an expression
  312.      is stored which (when evaluated) references the global.
  313.      Arbitrary objects may be defined as globals. (use the messages menu item &
  314.      look for implementors of addGlobalsTo:manager:).
  315.     The default is to define as global
  316.         globals in Smalltalk,
  317.         classes,
  318.         class variables & pool variables.
  319.     Collecting the globals takes about 2 seconds. If this is too much time per object
  320.     a default set of globals could be maintained in a class variable"
  321.  
  322.     Smalltalk addGlobalsTo: globals manager: self
  323.  
  324.     "MessageTally spyOn: [(BinaryOutputManager new: 2) initialize]
  325.  
  326.      Time millisecondsToRun: [(BinaryOutputManager new: 2) initialize]"! !
  327.  
  328. !BinaryOutputManager methodsFor: 'accessing'!
  329.  
  330. putIdOf: anObject on: aStream
  331.     | objectId owner |
  332.     anObject hasSpecialBinaryRepresentation ifTrue: [
  333.         ^anObject storeBinaryOn: aStream manager: self].
  334.     nil == (objectId _ self findValueOrNil: anObject)
  335.         ifFalse: [^aStream nextPut: IdType; nextNumber: 3 put: objectId].
  336.     (owner _ globals at: anObject ifAbsent: []) == nil
  337.         ifTrue: [
  338.             self at: anObject put: (lastIndex _ lastIndex + 1).
  339.             aStream
  340.                 nextPut: ObjectType;
  341.                 nextNumber: 3 put: lastIndex.
  342.             anObject storeBinaryDefinitionOn: aStream manager: self]
  343.         ifFalse: [
  344.             anObject isClass ifTrue: [^self putIdOfClass: anObject on: aStream].
  345.             self at: anObject put: (lastIndex _ lastIndex + 1).    
  346.             aStream
  347.                 nextPut: GlobalType;
  348.                 nextNumber: 3 put: lastIndex.
  349.             owner storeBinaryDefinitionOf: anObject on: aStream manager: self]!
  350.  
  351. putIdOfClass: anObject on: aStream
  352.     | classId |
  353.     nil == (classId _ self findValueOrNil: anObject)
  354.         ifFalse: [^aStream nextPut: IdType; nextNumber: 3 put: classId].
  355.     self at: anObject put: (lastIndex _ lastIndex + 1).
  356.     aStream
  357.         nextPut: ClassType;
  358.         nextNumber: 3 put: lastIndex.
  359.     anObject storeBinaryDefinitionOn: aStream manager: self! !
  360.  
  361. !BinaryOutputManager methodsFor: 'private'!
  362.  
  363. findValueOrNil: key  
  364.     "Look for the key in the receiver.  If it is found, answer
  365.     the value corresponding to the key, otherwise answer nil."
  366.  
  367.     | index length probe pass |
  368.     length _ self basicSize.
  369.     pass _ 1.
  370.     index _ key identityHash \\ length + 1.
  371.     [(probe _ self basicAt: index) == nil ifTrue: [^nil].
  372.     probe == key]
  373.         whileFalse: [
  374.             (index _ index + 1) > length ifTrue: 
  375.                 [index _ 1.
  376.                 pass _ pass + 1.
  377.                 pass > 2 ifTrue: [^nil]]].
  378.     ^(valueArray basicAt: index)! !
  379. "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
  380.  
  381. BinaryOutputManager class
  382.     instanceVariableNames: ''!
  383.  
  384.  
  385. !BinaryOutputManager class methodsFor: 'binary storage'!
  386.  
  387. store: anObject on: aStream
  388.     | manager fileStream |
  389.     Cursor wait showWhile: [manager _ (self new: 1024) initialize].
  390.     Cursor write showWhile: [
  391.         (aStream isKindOf: String)
  392.             ifTrue: [
  393.                 fileStream _ FileStream fileNamed: aStream.
  394.                 fileStream binary.
  395.                 anObject storeBinaryOn: fileStream manager: manager.
  396.                 fileStream close]
  397.             ifFalse: [
  398.                 anObject storeBinaryOn: aStream manager: manager]]! !
  399.  
  400.  
  401. !ClassDescription methodsFor: 'binary storage'!
  402.  
  403. binaryDefinitionFrom: stream manager: manager
  404.     | obj basicSize i |
  405.     self isPointers ifTrue: [
  406.         stream next. "skip instSize"
  407.         ^self isVariable
  408.             ifTrue: [self basicNew: (stream nextNumber: 3)]
  409.             ifFalse: [self basicNew]].
  410.  
  411.     obj _ self basicNew: (basicSize _ stream nextNumber: 4).
  412.     i _ 0.
  413.     self isBytes
  414.         ifTrue: [
  415.             [(i _ i + 1) <= basicSize] whileTrue: [
  416.                 obj basicAt: i put: stream next]]
  417.         ifFalse: [
  418.             [(i _ i + 1) <= basicSize] whileTrue: [
  419.                 obj basicAt: i put: stream nextWord]].
  420.     ^obj!
  421.  
  422. storeBinaryDefinitionOn: stream manager: manager
  423.     | myName |
  424.     stream
  425.         nextWordPut: (format bitAnd: 16rFFFF);
  426.         nextWordPut: (myName _ self name) size.
  427.     myName do: [:c| stream nextPut: c asciiValue]! !
  428.  
  429.  
  430. !Set methodsFor: 'binary storage'!
  431.  
  432. readBinaryContentsFrom: stream manager: manager
  433.     super readBinaryContentsFrom: stream manager: manager.
  434.     self rehash! !
  435.  
  436.  
  437. !UndefinedObject methodsFor: 'binary storage'!
  438.  
  439. hasSpecialBinaryRepresentation
  440.     ^true!
  441.  
  442. storeBinaryOn: stream manager: manager
  443.     stream nextPut: manager codeForNil! !
  444.  
  445.  
  446. !Class methodsFor: 'testing'!
  447.  
  448. isClass
  449.     ^true! !
  450.  
  451. !Class methodsFor: 'binary storage'!
  452.  
  453. addGlobalsTo: globalDictionary manager: manager
  454.     classPool == nil ifFalse: [
  455.         classPool associationsDo: [:assoc|
  456.             globalDictionary at: assoc put: self]]!
  457.  
  458. storeBinaryDefinitionOf: anAssociation on: stream manager: manager
  459.     | string | 
  460.     string _ self name, ' classPool at: ', anAssociation key storeString.
  461.     stream nextNumber: 2 put: string size.
  462.     string do: [:char| stream nextPut: char asciiValue]! !
  463.  
  464.  
  465. !Boolean methodsFor: 'binary storage'!
  466.  
  467. hasSpecialBinaryRepresentation
  468.     ^true! !
  469.  
  470.  
  471. !FileStream methodsFor: 'testing'!
  472.  
  473. isFileStream
  474.     ^true! !
  475.  
  476.  
  477. !String class methodsFor: 'binary storage'!
  478.  
  479. binaryDefinitionFrom: stream manager: manager
  480.     ^(stream next: (stream nextNumber: 4)) asString! !
  481.  
  482. BinaryIOManager variableSubclass: #BinaryInputManager
  483.     instanceVariableNames: 'stream '
  484.     classVariableNames: ''
  485.     poolDictionaries: ''
  486.     category: 'System-Support'!
  487. BinaryInputManager comment:
  488. 'I read binary files of the format created by BinaryOutputManager.  See the comment there for details of the format.  Use
  489.  
  490.     BinaryInputManager readFrom: ''filename.stbin''
  491.  
  492. to recreate the objects stored on such files.'!
  493.  
  494.  
  495. !BinaryInputManager methodsFor: 'public access'!
  496.  
  497. readFrom: aStream
  498.     (stream _ aStream) isFileStream
  499.         ifTrue: [stream binary].
  500.     ^self nextObject! !
  501.  
  502. !BinaryInputManager methodsFor: 'structure reading'!
  503.  
  504. getClassDefinition
  505.     | id format nameLength name class |
  506.     id _ stream nextNumber: 3.
  507.     format _ stream nextNumber: 2.
  508.     nameLength _ stream nextNumber: 2.
  509.     name _ (stream next: nameLength) asString.
  510.     (Symbol hasInterned: name ifTrue: [:sym| name _ sym])
  511.         ifFalse: [self error: 'Unknown class name: ', name].
  512.     class _ Smalltalk at: name ifAbsent: [self error: 'Non-existant class: ', name].
  513.     (class format bitAnd: 16rFFFF) ~= format
  514.         ifTrue: [self error: 'Class format has changed'].
  515.     self at: id put: class.
  516.     ^class!
  517.  
  518. getFalse
  519.     ^false!
  520.  
  521. getGlobalDefinition
  522.     | id nameLength object |
  523.     id _ stream nextNumber: 3.
  524.     nameLength _ stream nextNumber: 2.
  525.     object _ Cursor execute showWhile: [
  526.                     Compiler evaluate: (stream next: nameLength) asString for: nil logged: false].
  527.     ^self at: id put: object!
  528.  
  529. getNil
  530.     ^nil!
  531.  
  532. getObjectDefinition
  533.     | id class obj |
  534.     self
  535.         at: (id _ stream nextNumber: 3)
  536.         put: (obj _ (class _ self nextObject)
  537.                         binaryDefinitionFrom: stream manager: self).
  538.     "Must add the object to the table BEFORE reading the rest of its definition
  539.      because it may (even indirectly) refer to itself"
  540.     class isPointers ifTrue: [obj readBinaryContentsFrom: stream manager: self].
  541.     ^obj!
  542.  
  543. getObjectId
  544.     | id |
  545.     ^self at: (id _ stream nextNumber: 3) ifAbsent: [self error: 'non-existant object id']!
  546.  
  547. getTrue
  548.     ^true!
  549.  
  550. nextObject
  551.     | typeByte |
  552.     (typeByte _ stream next) > 127 ifTrue: [
  553.         stream skip: -1.
  554.         ^SmallInteger binaryDefinitionFrom: stream manager: self].
  555.  
  556.     ^self perform: (TypeTable at: typeByte)! !
  557. "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
  558.  
  559. BinaryInputManager class
  560.     instanceVariableNames: ''!
  561.  
  562.  
  563. !BinaryInputManager class methodsFor: 'structure reading'!
  564.  
  565. readFrom: streamOrFileName
  566.  
  567.     "Reads an object's structure from the stream streamOrFileName
  568.      or the file named streamOrFileName"
  569.  
  570.     (streamOrFileName isKindOf: String)
  571.         ifTrue:
  572.             [^Cursor read showWhile: [(self new: 1024) readFrom: (FileStream fileNamed: streamOrFileName)]].
  573.     ^(self new: 1024) readFrom: streamOrFileName! !
  574.  
  575.  
  576. !Dictionary methodsFor: 'binary storage'!
  577.  
  578. addGlobalsTo: globalDictionary manager: manager
  579.     self associationsDo: [:assoc| globalDictionary at: assoc put: self]!
  580.  
  581. storeBinaryDefinitionOf: anObject on: stream manager: manager
  582.     | string | 
  583.     string _ (Smalltalk keyAtValue: self), ' associationAt: ', anObject key storeString.
  584.     stream nextNumber: 2 put: string size.
  585.     string do: [:char| stream nextPut: char asciiValue]! !
  586.  
  587.  
  588. !True methodsFor: 'binary storage'!
  589.  
  590. storeBinaryOn: stream manager: manager
  591.     stream nextPut: manager codeForTrue! !
  592.  
  593.  
  594. !False methodsFor: 'binary storage'!
  595.  
  596. storeBinaryOn: stream manager: manager
  597.     stream nextPut: manager codeForFalse! !
  598.  
  599.  
  600. !SystemDictionary methodsFor: 'binary storage'!
  601.  
  602. addGlobalsTo: globalDictionary manager: manager
  603.     | pools |
  604.     pools _ Set new.
  605.     self associationsDo: [:assoc|
  606.         assoc value isClass
  607.             ifTrue: [
  608.                 assoc value addGlobalsTo: globalDictionary manager: manager.
  609.                 pools addAll: assoc value sharedPools]
  610.             ifFalse: [
  611.                 globalDictionary at: assoc put: self].
  612.         globalDictionary at: assoc value put: self].
  613.  
  614.     pools do: [:poolDictionary|
  615.         poolDictionary addGlobalsTo: globalDictionary manager: manager]!
  616.  
  617. storeBinaryDefinitionOf: anObject on: stream manager: manager
  618.     | string | 
  619.     string _ anObject class == Association
  620.                 ifTrue: ['Smalltalk associationAt: ', anObject key storeString]
  621.                 ifFalse: ['Smalltalk at: ', (self keyAtValue: anObject) storeString].
  622.     stream nextNumber: 2 put: string size.
  623.     string do: [:char| stream nextPut: char asciiValue]! !
  624.  
  625.  
  626. !Symbol class methodsFor: 'binary storage'!
  627.  
  628. binaryDefinitionFrom: stream manager: manager
  629.     ^self intern: (super binaryDefinitionFrom: stream manager: manager)! !
  630.